home *** CD-ROM | disk | FTP | other *** search
/ Workbench Add-On / Workbench Add-On - Volume 1.iso / Dev / Oberon / texts / SymbolFiles.Text < prev    next >
Text File  |  1994-02-09  |  55KB  |  1,367 lines

  1. Departement Informatik
  2. Institut für Computersysteme
  3. Eidgenössische Technische Hochschule
  4. Zürich
  5.  
  6. Robert Griesemer
  7. On the Linearization of Graphs and Writing Symbol Files
  8.  
  9. Cuno Pfister (ed.)
  10. Oberon Technical Notes
  11. Beat Heeb
  12. Josef Templ
  13. March 1991
  14.  
  15. Address of the authors:
  16.   Computersysteme
  17.   ETH-Zentrum
  18.   CH-8092 Zurich, Switzerland
  19.  
  20. e-mail:
  21.   griesemer@inf.ethz.ch
  22.   pfister@inf.ethz.ch
  23.  
  24. Copyright (c) 1991 Departement Informatik, ETH Zürich
  25.  
  26. On the Linearization of Graphs and Writing Symbol Files
  27. Robert Griesemer
  28.  
  29. Abstract
  30.  
  31. The linearization of general graphs represented by pointer and record
  32. data structures is a problem often arising in computer programs.
  33. Whenever a graph has to be stored on or transmitted over a sequentially
  34. organized carrier, a form of linearization is used. A simple algorithm
  35. for this purpose is presented and a special application - the writing of
  36. symbol files as required by modern language compilers - is described in
  37. more detail.
  38.  
  39. Keywords: Linearization, Graphs, Symbol Files.
  40.  
  41. 1. Linearization of Graphs
  42.  
  43. General graphs occur in various forms in computer science, sophisticated
  44. data structures may often be interpreted as graphs. Whenever such a data
  45. structure has to be stored on a file or has to be transmitted over a
  46. network, the linearization problem occurs. For special forms of
  47. non-linear data structures (e.g. trees) well-known solutions exist and
  48. are comprehensively described in the basic literature. Nevertheless, for
  49. more general data structures the wheel has to be reinvented and
  50. literature is difficult to find [ReMö86]. The problem has a twofold
  51. nature: firstly, the graph has to be linearized by means of a write
  52. algorithm , and secondly, it has to be rebuilt out of its linear
  53. description by a read algorithm . In the following, linearization means
  54. writing a graph to a file.
  55.  
  56. 1.1 Preconditions
  57.  
  58. First of all, we remember that every general (undirected) graph may be
  59. represented by a directed graph, by means of having two directed edges
  60. instead of an undirected one. Hence, we concentrate on directed graphs
  61. only. Secondly, we consider only rooted and connected graphs; i.e.
  62. graphs with a special root node and a path from the root to every other
  63. node. Unconnected graphs or graphs with several root nodes are easily
  64. extended such, that they obey the above preconditions. Thirdly, as an
  65. (academic) restriction only finite graphs are considered.
  66.  
  67. In computer programs, graphs may be represented in various forms,
  68. depending on the available notational support (the programming language)
  69. and the way the data structure is used (the program). Here we consider
  70. only graphs described in terms of pointers and records; i.e. every graph
  71. node is represented by a record and every edge is represented by a
  72. pointer. Note that possible information attached to the edges of a graph
  73. ( labeled edges ) may be interpreted as additional node data.
  74.  
  75. The nodes of such a graph may not all have the same type; i.e. the
  76. amount of data in every node may be different and the number of directed
  77. edges to other nodes may vary. It depends on the application and
  78. available language how different nodes are specified. For the sake of
  79. simplicity we identify each node with a positive tag -number (> 0), so
  80. that every node type is clearly determined by its tag and vice versa.
  81. Then, every node contains a certain amount M(tag) of data and (at most)
  82. a certain number N(tag) of directed edges to other nodes. Hence, a
  83. general graph node and its edges may be described in the following way
  84. (written in Oberon [Wi88]):
  85.  
  86. TYPE
  87.   Node = POINTER TO NodeDesc;
  88.  
  89.   NodeDesc = RECORD
  90.     tag: INTEGER;                  (* determines node type; tag > 0 *)
  91.     data: ARRAY M(tag) OF INTEGER; (* M depends on the node type (tag) *)
  92.     link: ARRAY N(tag) OF Node     (* N depends on the node type (tag) *)
  93.   END;
  94.  
  95. Note that any data structure represented in any way in computer memory
  96. may be written to a file by simply writing out sequentially the
  97. corresponding memory area.  Reading requires "only" the data to be read
  98. into the same memory area (otherwise pointers would be incorrect).  But
  99. normally this is an inappropriate solution for several reasons: often
  100. the data structure is distributed over the entire available memory and
  101. writing would lead to an immense waste of space.  For reading, the
  102. destination memory addresses must be specified which is almost never
  103. possible and a file created this way is inherently not portable (to
  104. another computer system).
  105.  
  106. Hence, writing of graphs requires pointers to be transformed into
  107. another form of reference and vice versa for reading.  In addition,
  108. reading and writing should be as efficient as possible considering both
  109. memory and time; e.g. each node description should appear once and only
  110. once on the file.
  111.  
  112. 1.2 The Write Algorithm
  113.  
  114. The write algorithm resembles closely a naive recursive mark-algorithm
  115. for garbage collectors, actually it is nearly the same task to be done:
  116. all nodes have to be traversed and marked; marking is necessary to avoid
  117. a second traversal and to refer to the node's first occurence. While
  118. traversing the graph its structure is written to a file. Hence, the node
  119. data structure has to be extended by a mark field, which initially must
  120. be zero:
  121.  
  122. TYPE
  123.   Node = POINTER TO NodeDesc;
  124.  
  125.   NodeDesc = RECORD
  126.     mark: INTEGER;            (* used for linearization; initially = 0 *)
  127.     tag: INTEGER;                  (* determines node type; tag > 0 *)
  128.     data: ARRAY M(tag) OF INTEGER; (* N depends on the node type (tag) *)
  129.     link: ARRAY N(tag) OF Node     (* M depends on the node type (tag) *)
  130.   END;
  131.  
  132. We say a node q is marked iff q.mark > 0. The WriteNode procedure (see
  133. below) traverses the graph in pre-order, starting with the root node.
  134. Whenever an unmarked node is encountered, the node is numbered and thus
  135. marked (line 4), the node tag and data are written (lines 4 and 5) and
  136. its successor nodes are traversed (line 6). Note that a node must be
  137. numbered before its subtrees are traversed because they may refer to it.
  138. Numbering is done using the counter NofNodes which is one initially and
  139. is then incremented by one with every processed node. Hence, NofNodes is
  140. always greater than zero. Whenever an already marked node is traversed,
  141. only its negative node number is written out as reference number (line
  142. 2). If the node doesn't exist (i.e. q = NIL) zero is written out (line
  143. 1):
  144.  
  145. VAR
  146.   NofNodes: INTEGER; (* node number; initially = 1 *)
  147.  
  148. PROCEDURE WriteNode(q: Node);
  149.   VAR i: INTEGER;
  150. BEGIN
  151. (1) IF q = NIL THEN WriteInt(0)
  152. (2) ELSIF q.mark > 0 THEN (* already marked *) WriteInt(-q.mark)
  153. (3) ELSE (* first occurence *)
  154. (4) WriteInt(q.tag); q.mark := NofNodes; INC(NofNodes);
  155. (5) i := 0; WHILE i < M(tag) DO WriteInt(q.data[i]); INC(i) END;
  156. (6) i := 0; WHILE i < N(tag) DO WriteNode(q.link[i]); INC(i) END
  157. (7) END
  158. END WriteNode;
  159.  
  160. During execution of WriteNode with argument root all nodes are numbered
  161. in the order of their first occurence. References to already written
  162. nodes are the negative node numbers. While reading the file this
  163. information will be used to reconstruct the graph (see 1.3 The Read
  164. Algorithm). Before WriteNode can be called a second time for the same
  165. graph or parts of it, the preconditions have to be established again,
  166. i.e. the nodes must be unmarked. When using time-stamps, no such unmark
  167. pass is necessary (due to an idea of J. Templ, see [PfiHeTe91]: A
  168. Symmetric Solution to the Load/Store Problem ). The WriteNode procedure
  169. leads to the following file structure (in EBNF, terminal symbols are
  170. described in double quotes):
  171.  
  172.   Graph = NodeRef | NoNode | NodeDesc.
  173.  
  174.   NodeRef = "negative node number (< 0)".
  175.  
  176.   NoNode = "0".
  177.  
  178.   NodeDesc = "node tag (> 0)" "node data" {Graph}.
  179.  
  180. It is obvious that the algorithm terminates for all graphs: there is
  181. only a finite number of nodes and every procedure call works on at least
  182. one node. The recursion is stopped when an already marked node and hence
  183. a loop is found (line 2) and the algorithm returns to its predecessor
  184. node. In line 4 the assignment q.mark := NofNodes is executed only if
  185. q.mark = 0, i.e. each node is numbered at most once (because NofNodes >
  186. 0). On the other hand, since after numbering of the node q^ (line 4)
  187. WriteNode numbers all subgraphs of q^ (line 6), each node is numbered at
  188. least once. In combination we may conclude that each node is marked
  189. exactly once. Finally, because each node's data is written iff the node
  190. was numbered immediatly before (line 5), it becomes clear that each node
  191. is written only once.
  192.  
  193. Note that WriteNode is a one-pass algorithm and that no additional data
  194. structures except NofArgs and the procedure activation stack are
  195. required. The run time complexity is O(n) where n is the number of edges
  196. in the graph. As we mentioned above, WriteNode resembles closely the
  197. mark phase of a mark-and-sweap garbage collector, therefore it is
  198. possible to transform the algorithm into a completely iterative form
  199. (e.g. if stack space is critical). The analoguous transformations for a
  200. simple garbage collector are described in [PfiHeTe91].
  201.  
  202. 1.3 The Read Algorithm
  203.  
  204. The read algorithm reconstructs a (sub-) tree from its description on a
  205. file. Each node block in the file starts with an identification tag.
  206. According to the EBNF file structure there are three cases to
  207. distinguish: the node tag may be zero, negative or positive (excluding
  208. zero).
  209.  
  210. VAR
  211.   NofNodes: INTEGER; (* node number; initially = 1 *)
  212.   NodeTab: ARRAY MaxNodes OF Node; (* node table; NodeTab[0] = NIL *)
  213.  
  214. PROCEDURE ReadNode(VAR q: Node);
  215. VAR tag, i: INTEGER;
  216. BEGIN
  217. (1) ReadInt(tag);
  218. (2) IF tag <= 0 THEN (* node reference *) q := NodeTab[-tag]
  219. (3) ELSE (* first occurence *)
  220. (4)   NEW(q, tag); NodeTab[NofNodes] := q; INC(NofNodes);
  221. (5)   i := 0; WHILE i < M(tag) DO ReadInt(q.data[i]); INC(i) END;
  222. (6)   i := 0; WHILE i < N(tag) DO ReadNode(q.link[i]); INC(i) END
  223. (7) END
  224. END ReadNode;
  225.  
  226. The first and second case are handled together by initializing the
  227. (otherwise unused) NodeTab entry zero to NIL. Because an empty subtree
  228. is identified by a zero tag, q then automatically becomes NIL (line 2).
  229. A node that occurs for the first time is identified by a positive number
  230. which is also its node tag. Then, such a node is created using NEW and
  231. stored in a global node table NodeTab (line 4). Note again that this
  232. assignment must be done before any subtrees are read (they may
  233. potentially refer to it). After creation of the new node its data and
  234. its subtrees are read (line 5 and 6). A negative node tag refers to an
  235. already read node, with the node number -tag. This node is obtained from
  236. the NodeTab array (line 2).
  237.  
  238. It should be clear that this algorithm rebuilds the original graph, as
  239. each line in ReadNode has its counterpart in WriteNode and each call of
  240. WriteNode during writing implies a corresponding call of ReadNode during
  241. reading. Clearly this algorithm is also O(n) where n is the number of
  242. edges in the graph. A temporary node array of size n is used for
  243. reading, this might be a drawback in case of very large graphs. A 2-pass
  244. algorithm which needs temporary storage only for nodes which are
  245. referenced more than once is described in the appendix.
  246.  
  247. 2. Writing Symbol Files
  248.  
  249. Today's modular programming languages like Modula-2, Ada, Oberon and
  250. others allow an application to be programmed in several more or less
  251. independent parts, so-called modules (or packages). Such a module
  252. typically defines data structures and provides operations (procedures)
  253. on them, these exported objects may be used ( imported ) by other
  254. modules without knowledge of their implementation.
  255.  
  256. Therefore, the information about a module's interface has to be
  257. available to the compiler in an efficient way: in Modula-2 and Oberon
  258. the necessary data is recorded on so-called symbol files. For
  259. historical reasons and to avoid confusion we use the term symbol file
  260. for any linear data structure which describes a module's interface.
  261. Actually, it is not necessary that symbol files are represented by a
  262. separate file (see 2.4 Implementation Aspects).
  263.  
  264. During compilation, the information about a module's interface is held
  265. in the symbol table of the compiler. The symbol table can be regarded as
  266. a graph, hence writing a symbol file requires linearizing the necessary
  267. partial graph of this table. The methods described in the following have
  268. been implemented in a compiler for an experimental Oberon-like language
  269. [Gri90]. The code fragments detail only the principal structure, a
  270. complete implementation may be found in the appendix.
  271.  
  272. 2.1 Structure of Symbol Tables
  273.  
  274. The symbol table of a compiler for an Oberon-like language describes the
  275. compiled objects, which are constants, types, variables, procedures, or
  276. modules. The table itself is built when processing declarations. These
  277. may be nested, so the compiler has to manage a stack of scopes, i.e.
  278. visibility ranges of objects.  For our purposes, it is sufficient to
  279. store the objects of a scope in a linear list. More sophisticated
  280. implementations would use structures like binary trees, because objects
  281. have to be searched efficiently during compilation.  In Modula-2 and
  282. Oberon only global objects may be exported, i.e. only objects within the
  283. global scope of the symbol table have to be considered for export (Fig.
  284. 1).  Hence, writing the symbol file means linearizing the partial graph
  285. described by the exported (and therefore in some way marked) objects of
  286. this scope.
  287.  
  288. Fig. 1
  289.  
  290. Global Scope
  291.  
  292. Each node represents an object of the compiled program, containing all
  293. the necessary information about it, such as its name, the object kind,
  294. possibly an address and its type. Object types itself may have a very
  295. complex structure and are further described using a Struct data
  296. structure, which again may refer to other Struct nodes [Wi85, Cre90].
  297. Hence objects and types are described with two different record
  298. structures:
  299.  
  300. CONST
  301.   (* object modes *)
  302.   Undef* = 0; Scope = 1; Const* = 2; Type* = 3; Var* = 4; VarPar* = 5;
  303.   XVar* = 6; IVar* = 7; Field* = 8; LProc* = 9; XProc* = 10; IProc* = 11;
  304.   SProc* = 12; Mod* = 13;
  305.  
  306.   (* type forms *)
  307.   Char* = 2; Bool* = 3; SInt* = 4; Int* = 5; LInt* = 6; Set* = 7;
  308.   Real* = 8; LReal* = 9; Cmplx* = 10; LCmplx* = 11; NilTyp* = 13;
  309.   NoTyp* = 14; Proc* = 15; String* = 16; Array* = 17; DynArr* = 18;
  310.   Record* = 19; Pointer* = 20;
  311.  
  312. TYPE
  313.   Name* = ARRAY 32 OF CHAR;
  314.   Object* = POINTER TO ObjectDesc;
  315.   Struct* = POINTER TO StructDesc;
  316.  
  317.   ObjectDesc* = RECORD
  318.     link*, next*: Object; (* objects are chained using next *)
  319.     name*: Name;
  320.     typ*: Struct;
  321.     marked*: BOOLEAN; (* marked objects are exported *)
  322.     mode*: INTEGER; (* identifies object kind *)
  323.     mnolev*: INTEGER; (* module numbers are <= 0 *)
  324.     ...
  325.     (* object specific data *)
  326.   END;
  327.  
  328.   StructDesc* = RECORD
  329.     ref: INTEGER; (* used as mark field *)
  330.     form*: INTEGER; (* identifies structure kind *)
  331.     obj*: Object; (* points to type object if it exists *)
  332.     len*, size*: LONGINT;
  333.     base*: Struct; (* result-, element-, base- or pointee type *)
  334.     link*: Object (* record scope *)
  335.   END;
  336.  
  337. Struct nodes describe the type of an object (array, record, pointer,
  338. procedure); a few types are predefined (e.g. Char, Integer, Real).
  339. Because types may be recursively defined, the resulting data structure
  340. may contain cycles. Many objects may have the same type and therefore
  341. refer to the same struct node.
  342.  
  343. 2.2 Export
  344.  
  345. The graph linearization algorithm in the form described in section 1
  346. actually works for different node kinds (determined by the tag field)
  347. but requires that all nodes are described using the same record.
  348. However, enforcing this precondition would have a far too strong impact
  349. on the structure of a compiler.  As we have actually two different
  350. record types for object and type description, the adequate solution is
  351. to have two sets of read and write procedures, one set for objects and
  352. one for types.  This distinction is even more justified by the fact that
  353. objects are stored in a simple linear list and are referenced only once
  354. (with the exception of type and module objects) while type descriptors
  355. may be referenced several times and potentially belong to cycles.
  356. References from struct nodes to their type objects are handled directly
  357. in the WriteStruct procedure.  Modules are never marked for export and
  358. written using a special procedure.  As a consequence, the write
  359. procedure which traverses the object scope does not have to take care of
  360. objects already traversed and therefore no marking is necessary.  Hence,
  361. the write procedure degenerates to a simple list traversal while for the
  362. corresponding read procedure no temporary array is necessary.  Using the
  363. above definitions, the WriteObjects procedure can be written as follows
  364. (primitive operations like WriteInt and WriteName may be found in the
  365. appendix section):
  366.  
  367. PROCEDURE WriteObjects(obj: Object);
  368. BEGIN
  369.   WHILE obj # NIL DO
  370.     IF obj.marked THEN
  371.       WriteInt(obj.mode);
  372.       IF (obj.mode # Type) OR (obj.typ.obj # obj) THEN
  373.         (* no-type or alias type *)
  374.         WriteName(obj.name)
  375.       ELSE (* other type *) Write(0X)
  376.       END;
  377.       WriteStruct(obj.typ);
  378.       IF obj.mode = Const THEN (* write const value *)
  379.       ELSIF obj.mode = LProc THEN (* write parameter list *)
  380.       ...
  381.       END
  382.     END;
  383.     obj := obj.next
  384.   END;
  385.   WriteInt(Undef) (* termination tag *)
  386. END WriteObjects;
  387.  
  388. For exported objects, the mode which describes the object kind, the
  389. object's name and its type are written.  As an optimization, the name of
  390. types is only written if it concerns alias types.  Otherwise, the name
  391. will be written by the WriteStruct procedure (given below).  Then,
  392. depending on the object mode, additional information is written (e.g.
  393. the value of constants or the parameter list of procedures).
  394.  
  395. The WriteStruct procedure closely resembles the Write algorithm
  396. described in 1.2 but is slightly complicated by the fact that named
  397. types (i.e. types for which a type object exists) have to be handled
  398. correctly.  Remember, that it is not correct to simply call the
  399. WriteObjects procedure, because WriteObjects is not built to handle more
  400. than one reference to an object. In addition, named types (and only
  401. these!) may be exported and imported over many modules and it must
  402. always be guaranteed that a type, whether it was imported via several
  403. modules ( indirect import ) or not, is described by one and only one
  404. struct node.  A unique identification is necessary, which is the type
  405. name combined with the description of the module where the type was
  406. defined first.  An analogous situation occurs when a type gets an alias
  407. name: then, the struct node always points to the first type object which
  408. defined the type.
  409.  
  410. VAR
  411.   nofStructs: INTEGER; (* structure number; initially = 1 *)
  412.  
  413. PROCEDURE WriteStruct(typ: Struct);
  414.   VAR name: Name;
  415. BEGIN
  416.   IF typ = NIL THEN WriteInt(0)
  417.   ELSIF typ.ref > 0 THEN (* already marked *) WriteInt(-typ.ref)
  418.   ELSE (* first occurence *)
  419.     WriteInt(typ.form); typ.ref := nofStructs; INC(nofStructs);
  420.     IF typ.obj # NIL THEN (* named type *)
  421.       name := typ.obj.name;
  422.       IF ~typ.obj.marked THEN (* invisible type *)
  423.         name[0] := CHR(ORD(name[0]) - ORD("@"))
  424.       END;
  425.       WriteName(name); WriteMod(GMod[-typ.obj.mnolev])
  426.     ELSE Write(0X)
  427.     END;
  428.     CASE typ.form OF
  429.     | Proc: (* write parameter list and result type *)
  430.     | Array: (* write element type and length *)
  431.     ...
  432.     END
  433.   END
  434. END WriteStruct;
  435.  
  436. Note that for exported named types there is a distinction between those
  437. with and those without corresponding exported type objects, where the
  438. latter are called invisible types. Invisible types must not be visible
  439. in an importing module, i.e. a programmer is not allowed to use them by
  440. name within a declaration. On the other hand they have to be visible to
  441. the compiler because it must be ensured that all invisible types with
  442. the same name are mapped onto a common struct node.  Hence, the same
  443. information as for named types is written, but a simple trick inhibits
  444. any use of the type name within a program: the first letter of its name
  445. (which is always greater or equal than "A") is modified such that the
  446. name becomes a syntactically invalid identifier.
  447.  
  448. For named types the declaring module has to be known. Because several
  449. types may be exported by the same module, the corresponding module
  450. object may be referenced more than once. A special procedure which
  451. handles modules correctly is used:
  452.  
  453. VAR
  454.   nofLMods: INTEGER; (* local module number; initially = 0 *)
  455.  
  456. PROCEDURE WriteMod(mod: Object);
  457. BEGIN
  458.   IF mod.ref < 0 THEN (* first occurence *)
  459.     mod.ref := nofLMods; INC(nofLMods);
  460.     WriteInt(Mod); WriteKey(mod.key); WriteName(mod.name)
  461.   ELSE WriteInt(-mod.ref)
  462.   END
  463. END WriteMod;
  464.  
  465. Like struct nodes, module descriptors are only written at their very
  466. first occurence. Whenever the same module is referenced later, only its
  467. reference number is written. Module pointers are never NIL, so numbering
  468. starts with zero and a module is marked iff mod.ref >= 0. During import
  469. the compiler has to check that only one version of a module is used
  470. globally, therefore every module needs a unique key. Remember that
  471. modules are never written out accidentally by the WriteObjects
  472. procedure, because they are never marked for export.
  473.  
  474. Writing the complete symbol file requires writing out the module
  475. descriptor of the compiled module (by means of WriteMod) followed by
  476. writing out all its exported objects (by means of WriteObjects).
  477.  
  478. 2.3 Import
  479.  
  480. Like the general ReadNode procedure is mirroring the structure of the
  481. WriteNode procedure, the import procedures are similar to the export
  482. procedures. This fact allows for easy extension, because additionally
  483. written data in an export procedure automatically leads to the
  484. corresponding read operations in the import procedure. Nevertheless, a
  485. few difficulties need to be mastered anyway.
  486.  
  487. In several situations an object may be imported more than once: the
  488. trivial case occurs when the same module is imported twice because of a
  489. substitution (or alias) name. One might expect that this special case
  490. should be handled by simply ignoring a second import; but actually a
  491. multiple import of objects has to be handled anyway, hence double import
  492. of entire modules is only a special case of a more general situation.
  493. Multiple import of an object normally occurs for type objects, when
  494. beeing imported indirectly across different modules. Consider the
  495. following situation: a module A exports a type (object) T which is used
  496. in a variable V of a module B. Module C which imports A and B
  497. consequentially also imports the type T from A and the variable V from B
  498. and hence once again the type T as type of V (Fig. 2).
  499.  
  500. Fig. 2
  501.  
  502. Double import
  503.  
  504. However, multiply loading objects or structures, if not detected, could
  505. lead to incorrect incompatibilities during type checking.  Therefore,
  506. each object which is read from the symbol file is discarded if it was
  507. already present in the symbol table.  Hence, each object is represented
  508. by its very first loaded instance which is called primary instance
  509. [Gu85].  In consequence, the ReadObjects procedure reads an object from
  510. the symbol file but the procedure InsertImport inserts it in the
  511. corresponding module scope only if the object (with the same name) has
  512. not already been imported.  As an optimization, note that only alias
  513. types have to be (additionally) inserted with InsertImport because their
  514. names differ from their type object names.  All other types are handled
  515. in the ReadStruct procedure.
  516.  
  517. PROCEDURE InsertImport(VAR obj: Object; scope: Object);
  518.   VAR p, q: Object;
  519. BEGIN
  520.   p := scope; q := scope.next;
  521.   WHILE q # NIL DO
  522.     IF q.name = obj.name THEN obj := q; RETURN END;
  523.     p := q; q := q.next
  524.   END;
  525.   obj.mnolev := scope.mnolev; p.next := obj
  526. END InsertImport;
  527.  
  528. PROCEDURE ReadObjects(scope: Object);
  529.   VAR mode: LONGINT; obj: Object; typ: Struct; name: Name;
  530. BEGIN
  531.   LOOP (* read all objects *)
  532.     ReadInt(mode);
  533.     IF mode = Undef THEN (* no more objects *) EXIT
  534.     ELSIF mode = Type THEN
  535.       ReadName(name);
  536.       IF name # "" THEN (* alias type *)
  537.         NewObject(obj, name, Type); ReadStruct(obj.typ);
  538.         InsertImport(obj, scope)
  539.       ELSE (* other types *) ReadStruct(typ)
  540.       END
  541.     ELSE
  542.       ReadName(name); NewObject(obj, name, SHORT(mode));
  543.       ReadStruct(obj.typ);
  544.       IF mode = Const THEN (* read const value *)
  545.       ELSIF obj.mode = LProc THEN (* read parameter list *)
  546.       ...
  547.       END;
  548.     InsertImport(obj, scope)
  549.     END
  550.   END
  551. END ReadObjects;
  552.  
  553. The procedure ReadStruct decides upon reading the first number form
  554. whether the structure was already read from the (same) symbol file or
  555. not. In the first case, the structure already built is taken out of a
  556. local structure table LStruct which serves as a translation table for
  557. structure references analogous to NodeTab in the ReadNode procedure. In
  558. the second case, the structure is created and inserted in the LStruct
  559. table, then the specific structure information is read. As described in
  560. ReadObjects, named types must also be ignored if occuring a second time:
  561. the structure information is read but then discarded (by means of
  562. InsertImport) and the primary instance is used (and also inserted in the
  563. LStruct table).
  564.  
  565. As a tricky point, notice further: Because each type (named or not) may
  566. refer to itself, it is absolutely necessary that the primary instance is
  567. found before any other types are read (which potentially refer to the
  568. same type and therefore would obtain the wrong structure out of the
  569. LStruct table). Hence, no other types must occur between the type tag of
  570. a named type and its identification, i.e. its name and its original
  571. module description. This rule corresponds to postulate 5 in [Gu85].
  572.  
  573. VAR
  574.   nofStructs: INTEGER;
  575.   (* structure number; initially = 1 *)
  576.   LStruct: ARRAY MaxNofStructs OF Struct;
  577.   (* local structure table; LStruct[0] = NIL *)
  578.  
  579. PROCEDURE ReadStruct(VAR typ: Struct);
  580.   VAR form: LONGINT; htyp: Struct; name: Name; obj, mod: Object;
  581. BEGIN
  582.   ReadInt(form);
  583.   IF form <= 0 THEN (* struct reference or NIL *) typ := LStruct[-form]
  584.   ELSE (* first occurence *)
  585.     NewStruct(htyp, SHORT(form)); ReadName(name);
  586.     IF name # "" THEN (* named type *)
  587.       NewObject(obj, name, Type); obj.marked := TRUE; obj.typ := htyp;
  588.       htyp.obj := obj; ReadMod(mod); InsertImport(obj, mod.link);
  589.       typ := obj.typ
  590.     ELSE typ := htyp
  591.     END;
  592.     LStruct[nofStructs] := typ; INC(nofStructs);
  593.     CASE form OF
  594.     | Proc: (* read parameter list and result type *)
  595.     | Array: (* read element type and length *)
  596.     ...
  597.     END
  598.   END
  599. END ReadStruct;
  600.  
  601. At the end, the ReadMod procedure is presented.  As expected, a local
  602. module table LMod is used as translation table for module references. In
  603. addition, because modules must always be represented by their primary
  604. instances, a global module table GMod is necessary, which is accessed in
  605. the InsertMod procedure.
  606.  
  607. VAR
  608.   nofGMods*: INTEGER; (* global module number; initially = 0 *)
  609.   GMod*: ARRAY MaxNofGMods OF Object; (* global module table *)
  610.  
  611. PROCEDURE InsertMod*
  612.   (VAR mod: Object; VAR name: ARRAY OF CHAR; key: LONGINT);
  613.   VAR i: INTEGER;
  614. BEGIN
  615.   i := 0;
  616.   WHILE (i < nofGMods) & (name # GMod[i].name) DO INC(i) END;
  617.   IF i < nofGMods THEN  (* module already imported *)
  618.     mod := GMod[i];
  619.     IF mod.key # key THEN err(150) (* key inconsistency *) END
  620.   ELSE
  621.     NewObject(mod, name, Mod); (* must not be visible in global scope *)
  622.     mod.key := key; mod.mnolev := -nofGMods;
  623.     OpenScope(mod.link, mod.mnolev); CloseScope; (* allocate own scope *)
  624.     GMod[nofGMods] := mod; INC(nofGMods)
  625.   END
  626. END InsertMod;
  627.  
  628. VAR
  629.   nofLMods: INTEGER; (* local module number; initially = 0 *)
  630.   LMod: ARRAY MaxNofLMods OF Object; (* local module table *)
  631.  
  632. PROCEDURE ReadMod(VAR mod: Object);
  633.   VAR ref, key: LONGINT; name: Name;
  634. BEGIN
  635.   ReadInt(ref);
  636.   IF ref > 0 THEN (* first occurence *)
  637.     ReadKey(key); ReadName(name);
  638.     InsertMod(mod, name, key);
  639.     LMod[nofLMods] := mod; INC(nofLMods)
  640.   ELSE mod := LMod[-ref]
  641.   END
  642. END ReadMod;
  643.  
  644. Importing a whole module requires reading the module (by means of
  645. ReadMod) followed by reading all exported objects of this module (by
  646. means of ReadObjects). Together there are only a few additional rules to
  647. the general graph algorithm to be observed:
  648.  
  649. 1. For types and modules , which both may be referenced several times
  650. within the same symbol file , a marking scheme and a translation table
  651. analogous to the general graph read/write algorithms is used.
  652.  
  653. 2. For named types and modules , which both may occur in several symbol
  654. files , the primary instance always must be used and inserted into the
  655. local translation tables. If the primary instance already exists, the
  656. remaining data must be read but then discarded. Repeated occurence of
  657. the same module is detected using a global module table, repeated
  658. occurence of the same named type is detected using its module and the
  659. corresponding module scope.
  660.  
  661. 3. As a consequence of the second rule, no other types must occur in the
  662. symbol file before name and module of a named type are specified.
  663.  
  664. 2.4 Implementation Aspects
  665.  
  666. Symbol File Representation
  667.  
  668. As mentioned in the beginning, symbol files need not to be represented
  669. by a separate file. Actually, a symbol file independent of the
  670. corresponding object file mirrors the fact that in Modula-2 and other
  671. languages the definition and the implementation of a module were
  672. compiled separately: the definition module was compiled into a symbol
  673. file and the implementation module into an object file. If exported
  674. objects are marked in some way within the implementation module (as in
  675. Oberon), a definition module and hence a separate symbol file is not
  676. necessary. It is more adequate to produce only a single file during
  677. compilation, which contains all the necessary information about the
  678. module including its interface description. For example, the
  679. (conventional) symbol file may be appended to the object file. The
  680. advantages are obvious: only a single file has to be distributed, this
  681. file is always self-contained and therefore consistent and it is
  682. possible to directly generate the interface specification out of an
  683. object file with a Browser tool. Should it be necessary to inhibit
  684. public use of a module (e.g. because it supports low-level features), it
  685. is easy to remove the symbol file from the object file and distribute
  686. the interface-less object file only.
  687.  
  688. Canonical Form for Symbol Files
  689.  
  690. When a module has to be recompiled for some reason without a change in
  691. its interface, the old module key should be used again in the symbol
  692. file. Otherwise all depending modules would also be invalidated and
  693. would have to be recompiled. A simple method to check whether a module's
  694. interface has changed or not is to bytewise compare the new symbol file
  695. against the old one. If it has not changed, the old key can be reused.
  696. This comparison method requires very stable symbol files: e.g. the
  697. ordering of the exported objects should have no effect on the symbol
  698. file. This is clearly not fulfilled in the implementation described
  699. above (which we've chosen for simplicity), because objects are ordered
  700. in the linear list according to their occurence in the module. Desired
  701. is a kind of canonical form for symbol files.
  702.  
  703. As we mentioned earlier, access to a special object in the symbol table
  704. should be as efficient as possible, so one could implement the table
  705. using binary trees instead of (unsorted) linear lists. Then, the objects
  706. could be written in alphabetical order to the symbol file using an
  707. in-order traversal of the tree. Symbol files in this canonical form are
  708. invariant to any changes in the ordering of a module's objects.
  709. Unfortunately this implies an undesired side effect which destroys the
  710. efficiency of binary trees: Importing a symbol file means inserting the
  711. imported objects in binary trees. Because the objects are alphabetically
  712. sorted, the symbol table tree degenerates to a linear list. Further,
  713. most of the objects in typical modules are known by import. In
  714. consequence, searching in the symbol table means actually searching in
  715. linear lists. Hence, the additional implementation effort for simple
  716. binary trees may be no longer justified.
  717.  
  718. The situation may be improved by modifing the proposed canonical form.
  719. Instead of writing all objects in alphabetical order, groups of objects
  720. of the same kind (with the same mode) are written alphabetically: first
  721. all constants, then the variables, then types, and so on. Within each
  722. group the objects are ordered and the group ordering is also specified.
  723. This is another canonical form which is also invariant against any
  724. permutations of exported objects. When imported, the trees will not
  725. completely degenerate but are decomposed into several partial lists. The
  726. result is at least a better balanced tree. Note that the addional effort
  727. of traversing the tree in several passes (for each object group) is only
  728. necessary during export; the more time critical import procedure is not
  729. at all affected.
  730.  
  731. Predefined Types
  732.  
  733. In several languages there exist predefined types which are known to the
  734. compiler. Such types are always exported using a fixed reference number.
  735. Before any object is imported, they are inserted into the local
  736. structure table by the import procedure (see Appendix B).
  737.  
  738. Increased Import Speed
  739.  
  740. As measurements show (see below), when reading is bytewise, the import
  741. speed highly depends on the symbol file length. Besides strings, most of
  742. the data on a symbol file are integers. Hence, a principal goal should
  743. be to reduce the space used to write a single integer number. Integers
  744. occur frequently as tag or reference numbers and most of them are very
  745. small (with an absolute value less than 64). Nevertheless also bigger
  746. integers should be managed easily. The ReadInt and WriteInt procedures
  747. described in [Te90] allow integers to be written in a
  748. machine-independent format which uses only one byte per number in most
  749. cases.
  750.  
  751. 2.5 Measurements
  752.  
  753. The following measurements show lengths and reading times of symbol
  754. files. The basic modules of the Oberon System are choosen as a typical
  755. "module mix". The method described here (used in module CCT) is compared
  756. to the method used in the existing portable Oberon compilers (module
  757. OPT, see [Cre90]) which is essentially the same method as described in
  758. [Gu85]. To be fair, the CCT method was adjusted such that about the same
  759. information per object was written out as with OPT (e.g. the address of
  760. each parameter of a procedure) but using a compactifying WriteInt
  761. procedure. The measurements were made on a Ceres-2 computer [He88] with
  762. a NS32532 CPU running at 25 Mhz clock speed.
  763.  
  764. In the left table the lengths of the symbol files in bytes are shown
  765. (OPT lengths are 100%). On average, the CCT symbol files are about 25%
  766. shorter than the corresponding OPT files. When the same symbol files are
  767. written using a non-compactifying WriteInt procedure in CCT (for
  768. addresses only), the files are about 8 % shorter (measurements not shown
  769. here). The right table shows the reading times in ms for each symbol
  770. file (OPT times are 100%). For this, each file was imported 100 times
  771. and only the pure file reading time without directory operations was
  772. measured and the average taken. The actual time spent in the import
  773. procedures is much higher because of directory accesses and may vary
  774. even for the same file.
  775.  
  776. Tab. 2
  777.  
  778. Further analysis of the measurements shows what was presumed, namely a
  779. practically linear dependency between the file lengths and their reading
  780. times (Tab. 2); the linear regression coefficient r is nearly 1.0 for
  781. both methods. Although the average reading time per byte in CCT is
  782. larger than in OPT, the shorter file lengths made up for this
  783. difference. For comparison, the values for pure file reading are also
  784. shown (the reading time per byte is the average measured time for this
  785. file mix and is only valid for short files in general). In every case
  786. the file length completely dominates other factors, so to improve
  787. importing speed shorter symbol files have to be achieved. But
  788. nevertheless, such an effort is only justified if the file system offers
  789. some kind of caching strategy for files already open. Otherwise the
  790. reading time for such short files is negligible compared to the
  791. directory access time. The import and export procedures in CCT are about
  792. 20 % shorter in source code size than the OPT procedures (Tab. 2).
  793.  
  794. 3.  Summary
  795.  
  796. As we have seen, the linearization algorithm for general graphs is very
  797. simple and easily adjusted to similar problems. In the example of symbol
  798. files it leads to a clean and understandable solution. The simplicity of
  799. the algorithm and the fact that only local invariants have to be
  800. considered, allows symbol files to be easily extended. The main
  801. difference between the algorithm described here and the one described in
  802. [Gu85] is that here a pre-order traversal instead of a post-order
  803. traversal is used. Using a post-order traversal, several postulates have
  804. to be guaranteed all the time, which complicate the algorithm.
  805. Nevertheless, cyclic references within types are a problem which has to
  806. be handled in a special way. Although the post-order algorithm requires
  807. no recursion for reading, the presented algorithm is faster in the
  808. average because symbol files are shorter and time used for reading in
  809. todays computers is determined mostly by the length of the files which
  810. are to be processed.
  811.  
  812. Acknowledgements
  813.  
  814. I would like to thank Josef Templ, Cuno Pfister, Clemens Szyperski and
  815. H. Mössenböck. Josef answered tricky questions about symbol files; he
  816. and Cuno worked as proof readers. H. Mössenböck added valuable comments
  817. to the modified algorithm in Appendix A. Not to forget, the entire paper
  818. was written using the excellent Write text editor of Clemens.
  819.  
  820. References
  821.  
  822. [Cre90] R. Crelier. OP2: A Portable Oberon Compiler . Computersysteme
  823. ETH Zürich, Technical Report No. 125, February 1990.
  824.  
  825. [Gri90] R. Griesemer. Seneca - A Language for Numerical Computations on
  826. Vectorcomputers . Conpar 90 Proceedings, Volume on special technical
  827. contributions, Zürich, September 1990.
  828.  
  829. [Gu85] J. Gutknecht. Compilation of Data Structures: A New Approach to
  830. Efficient Modula-2 Symbol Files . Computersysteme ETH Zürich, Technical
  831. Report No. 64, July 1985.
  832.  
  833. [PfiHeTe91] C. Pfister, B. Heeb, J. Templ. Oberon Technical Notes .
  834. Companion paper.
  835.  
  836. [ReMö86] P. Rechenberg, H. Mössenböck. An Algorithm for the Linear
  837. Storage of Dynamic Data Structures . Internal Paper, University of Linz,
  838. Austria, 1986.
  839.  
  840. [Te90] J. Templ. SPARC-Oberon. User's Guide and Implementation.
  841. Computersysteme ETH Zürich, Technical Report No. 133, June 1990.
  842.  
  843. [Wi85] N. Wirth. A Fast and Compact Compiler for Modula-2 .
  844. Computersysteme ETH Zürich, Technical Report No. 64, July 1985.
  845.  
  846. [Wi88] N. Wirth. The Programming Language Oberon . Software - Practice
  847. and Experience, 18, 7, July 1988 and Computersysteme ETH Zürich,
  848. Technical Report No. 143, November 1990.
  849.  
  850. Appendix A: A modified Linearization Algorithm
  851.  
  852. When working with rather large graphs consisting of several thousands or
  853. even millions of nodes, it might be impractical to use a translation
  854. table NodeTab of about the same size as the graph for reading. If only
  855. multiple referenced nodes had to be stored in the NodeTab array, this
  856. translation table could be much smaller. This can be achieved by a split
  857. of the write phase into two subphases. As a desirable side effect, after
  858. writing, all preconditions for writing are established again, i.e. no
  859. unmarking is necessary. The modifications are described shortly:
  860.  
  861. Writing :
  862.  
  863. In the first pass all nodes are traversed and the mark field is used as
  864. reference counter (procedure Mark). For the mark field of every
  865. (reachable) node the following holds: In the second pass, every node
  866. that is referenced more than once (i.e. mark > 1) is written using a
  867. special tag and its negative node number is stored in its mark field
  868. (which now again fulfills the preconditions for writing).
  869.  
  870. Reading:
  871.  
  872. A negative node tag designates an already read node. A positive node tag
  873. specifies a node which occurs only once (tag is even) or a node which
  874. will be referenced again (tag is odd) and therefore must be stored in
  875. the NodeTab array.
  876.  
  877. TYPE
  878.   Node = POINTER TO NodeDesc;
  879.   NodeDesc = RECORD
  880.     mark: INTEGER; (* used for linearization; initially < 0 *)
  881.     tag: INTEGER; (* determines node type; tag > 0 *)
  882.     data: ARRAY M(tag) OF INTEGER; (* N depends on the node type (tag) *)
  883.     link: ARRAY N(tag) OF Node (* M depends on the node type (tag) *)
  884.   END;
  885.  
  886. VAR
  887.   NofNodes: INTEGER; (* node number; initially = 1 *)
  888.   NodeTab: ARRAY MaxRefs OF Node;
  889.   (* node table; contains each node referenced more than once *)
  890.  
  891. PROCEDURE Mark(q: Node); (* Pass 1 *)
  892. (* precondition: q: q.mark < 0 *)
  893.   VAR i: INTEGER;
  894. BEGIN
  895.   IF q # NIL THEN
  896.     IF q.mark < 0 THEN (* first occurence *) q.mark := 1;
  897.     i := 0; WHILE i < Ntag DO Mark(q.link[i]); INC(i) END
  898.   ELSE INC(q.mark)
  899.   END
  900.   END
  901. END Mark;
  902. (* postcondition: q: q is marked *)
  903.  
  904. PROCEDURE WriteNode(q: Node); (* Pass 2 *)
  905. (* precondition: (q: q is marked) (NofNodes = 1) *)
  906.   VAR i: INTEGER;
  907. BEGIN
  908.   IF q = NIL THEN WriteInt(0)
  909.   ELSIF q.mark < 0 THEN (* already marked *) WriteInt(q.mark)
  910.   ELSE (* first occurence *)
  911.     IF q.mark = 1 THEN (* node occurs only once *)
  912.       WriteInt(q.tag*2); q.mark := -1
  913.     ELSE (* node is referenced several times *)
  914.       WriteInt(q.tag*2 + 1); q.mark := -NofNode; INC(NofNodes)
  915.     END;
  916.     i := 0; WHILE i < Mtag DO WriteInt(q.data[i]); INC(i) END;
  917.     i := 0; WHILE i < Ntag DO WriteNode(q.link[i]); INC(i) END
  918.   END
  919. END WriteNode;
  920. (* postcondition: q: q.mark < 0 *)
  921.  
  922. PROCEDURE ReadNode(VAR q: Node);
  923. (* precondition: (NodeTab[0] = NIL) (NofNodes = 1) *)
  924.   VAR tag, i: INTEGER;
  925. BEGIN
  926.   ReadInt(tag);
  927.   IF tag <= 0 THEN (* node reference *) q := NodeTab[-tag]
  928.   ELSE (* first occurence *)
  929.     NEW(q, tag DIV 2);
  930.     IF ODD(tag) THEN (* node is referenced several times *)
  931.       NodeTab[NofNodes] := q; INC(NofNodes)
  932.     END;
  933.     i := 0; WHILE i < Mtag DO ReadInt(q.data[i]); INC(i) END;
  934.     i := 0; WHILE i < Ntag DO ReadNode(q.link[i]); INC(i) END
  935.   END
  936. END ReadNode;
  937.  
  938. Appendix B: Import / Export in Detail
  939.  
  940. In the following an extract of a table handler with the complete import
  941. / export procedures is shown. A few points are specific to this
  942. implementation and hence commented accordingly.
  943.  
  944. CONST
  945.  
  946.   (* implementation restrictions *)
  947.  
  948.   MaxNofGMods = 32; MaxNofLMods = 24; MaxNofStructs = 256;
  949.  
  950.   (* object modes *)
  951.  
  952.   Undef* = 0; Scope = 1; Const* = 2; Type* = 3; Var* = 4; VarPar* = 5;
  953.   XVar* = 6; IVar* = 7; Field* = 8; LProc* = 9; XProc* = 10;
  954.   IProc* = 11; SProc* = 12; Mod* = 13;
  955.  
  956.   (* type forms *)
  957.  
  958.   Char* = 2; Bool* = 3; SInt* = 4; Int* = 5; LInt* = 6; Set* = 7;
  959.   Real* = 8; LReal* = 9; Cmplx* = 10; LCmplx* = 11; NilTyp* = 13;
  960.   NoTyp* = 14; Proc* = 15; String* = 16; Array* = 17; DynArr* = 18;
  961.   Record* = 19; Pointer* = 20;
  962.  
  963. TYPE
  964.  
  965.   Name*   = ARRAY 32 OF CHAR;
  966.   Object* = POINTER TO ObjectDesc;
  967.   Struct* = POINTER TO StructDesc;
  968.  
  969.   ObjectDesc* = RECORD
  970.     link*, next*: Object;  (* objects are chained using next *)
  971.     name*       : Name;
  972.     typ*        : Struct;
  973.     marked*     : BOOLEAN; (* marked objects are exported *)
  974.     leave*      : BOOLEAN;
  975.     mode*       : INTEGER; (* identifies object kind *)
  976.     mnolev*     : INTEGER; (* module numbers are <= 0 *)
  977.     a0*, a1*    : LONGINT; (* object specific data *)
  978.     b0*, b1*    : LONGINT  (* object specific data *)
  979.   END;
  980.  
  981.   StructDesc* = RECORD
  982.     ref        : INTEGER; (* used as mark field *)
  983.     form*      : INTEGER; (* identifies structure kind *)
  984.     obj*       : Object;  (* points to type object if it exists *)
  985.     len*, size*: LONGINT;
  986.     base*      : Struct;  (* result-, element-, base- or pointee type *)
  987.     link*      : Object   (* record scope *)
  988.   END;
  989.  
  990. VAR
  991.   system, universe: Object; (* predefined scopes *)
  992.   topScope*, undefObj*: Object; (* current topScope, error object *)
  993.   firstStructRef: INTEGER;
  994.   nofGMods*: INTEGER;
  995.   GMod*: ARRAY MaxNofGMods OF Object; (* global module table *)
  996.  
  997.   (* predefined types *)
  998.   undefTyp*, noTyp*, stringTyp*, boolTyp*, charTyp*, sIntTyp*, intTyp*,
  999.   lIntTyp*, setTyp*, realTyp*, lRealTyp*, cmplxTyp*, lCmplxTyp*: Struct;
  1000.  
  1001. PROCEDURE err(no: INTEGER);
  1002.   (* Displays an error message *)
  1003.  
  1004. (* general table handling *)
  1005.  
  1006. PROCEDURE NewObject*(VAR obj: Object; VAR name: ARRAY OF CHAR; mode: INTEGER);
  1007.   (* Creates a new object and initializes its fields *)
  1008.  
  1009. PROCEDURE NewStruct*(VAR str: Struct; form: INTEGER);
  1010.   (* Creates a new structure and initializes its fields *)
  1011.  
  1012. PROCEDURE OpenScope*(VAR scope: Object; mnolev: INTEGER);
  1013.   (* Opens a new scope if scope is NIL; otherwise the old scope is
  1014.      reopened *)
  1015.  
  1016. PROCEDURE CloseScope*;
  1017.   (* Closes topScope *)
  1018.  
  1019. PROCEDURE Insert*(VAR obj: Object; name: ARRAY OF CHAR; mode: INTEGER);
  1020.   VAR p, q: Object;
  1021. BEGIN
  1022.   p := topScope; q := topScope.next;
  1023.   WHILE q # NIL DO
  1024.     IF q.name = name THEN err(1) END;
  1025.     p := q; q := q.next
  1026.   END;
  1027.   NewObject(obj, name, mode); obj.mnolev := topScope.mnolev; p.next := obj
  1028. END Insert;
  1029.  
  1030. (* import table handling *)
  1031.  
  1032. PROCEDURE InsertMod*(VAR mod: Object; VAR name: ARRAY OF CHAR; key: LONGINT);
  1033.   VAR i: INTEGER;
  1034. BEGIN
  1035.   i := 0;
  1036.   WHILE (i < nofGMods) & (name # GMod[i].name) DO INC(i) END;
  1037.   IF i < nofGMods THEN  (* module already imported *)
  1038.     mod := GMod[i];
  1039.     IF mod.b0 # key THEN err(150) (* key inconsistency *) END
  1040.   ELSE
  1041.     NewObject(mod, name, Mod); (* must not be visible in global scope *)
  1042.     mod.b0 := key; mod.mnolev := -nofGMods;
  1043.     OpenScope(mod.link, mod.mnolev); CloseScope; (* allocate own scope *)
  1044.     IF nofGMods < MaxNofGMods THEN GMod[nofGMods] := mod; INC(nofGMods)
  1045.     ELSE err(227) (* to many imported modules *)
  1046.     END
  1047.   END
  1048. END InsertMod;
  1049.  
  1050. PROCEDURE InsertImport(VAR obj: Object; scope: Object);
  1051.   VAR p, q: Object;
  1052. BEGIN
  1053.   p := scope; q := scope.next;
  1054.   WHILE q # NIL DO
  1055.     IF q.name = obj.name THEN obj := q; RETURN END;
  1056.     p := q; q := q.next
  1057.   END;
  1058.   obj.mnolev := scope.mnolev; p.next := obj
  1059. END InsertImport;
  1060.  
  1061. (* import *)
  1062.  
  1063. PROCEDURE OpenRider(VAR R: Files.Rider; name: ARRAY OF CHAR; VAR res: INTEGER);
  1064. (* Sets a rider to the beginning of the symbol file *)
  1065.  
  1066. PROCEDURE Import*(VAR substName, impName, selfName: ARRAY OF CHAR);
  1067.   VAR
  1068.   R: Files.Rider;
  1069.   mod0, mod: Object;
  1070.   res, nofLMods, nofStructs: INTEGER;
  1071.   LMod: ARRAY MaxNofLMods OF Object;
  1072.   LStruct: ARRAY MaxNofStructs OF Struct;
  1073.  
  1074. PROCEDURE^ ReadStruct(VAR typ: Struct);
  1075.  
  1076. PROCEDURE ReadInt(VAR i: LONGINT);
  1077.   (* Reads integers written in a compacted form [Te90] *)
  1078.  
  1079.   VAR n: LONGINT; s: INTEGER; x: CHAR;
  1080.  
  1081. BEGIN
  1082.   s := 0; n := 0; Files.Read(R, x);
  1083.   WHILE ORD(x) >= 128 DO
  1084.     INC(n, ASH(ORD(x) - 128, s)); INC(s, 7); Files.Read(R, x)
  1085.   END;
  1086.   i := n + ASH(ORD(x) MOD 64 - ORD(x) DIV 64 * 64, s)
  1087. END ReadInt;
  1088.  
  1089. PROCEDURE ReadName(VAR name: ARRAY OF CHAR);
  1090.   (* Reads a name terminated with 0X *)
  1091.  
  1092. PROCEDURE ReadString(VAR pos, len: LONGINT);
  1093.   (* Reads a string terminated with 0X into the scanner string buffer *)
  1094.  
  1095. PROCEDURE ReadKey(VAR x: LONGINT);
  1096.   (* Reads an integer in uncompacted form *)
  1097.  
  1098. PROCEDURE ReadMod(VAR mod: Object);
  1099.   VAR ref, key: LONGINT; name: Name;
  1100. BEGIN
  1101.   ReadInt(ref);
  1102.   IF ref > 0 THEN (* first occurence *)
  1103.     ReadKey(key); ReadName(name);
  1104.     IF name = selfName THEN err(49) END;
  1105.     InsertMod(mod, name, key);
  1106.     IF nofLMods < MaxNofLMods THEN LMod[nofLMods] := mod; INC(nofLMods)
  1107.     ELSE err(227) (* to many imported modules *)
  1108.     END
  1109.   ELSE mod := LMod[-ref]
  1110.   END
  1111. END ReadMod;
  1112.  
  1113. PROCEDURE ReadFields(VAR field: Object);
  1114.   VAR obj, last: Object; name: Name;
  1115. BEGIN
  1116.   field := NIL;
  1117.   LOOP
  1118.     ReadName(name);
  1119.     IF name = "" THEN EXIT END;
  1120.     NewObject(obj, name, Field); ReadStruct(obj.typ); ReadInt(obj.a0);
  1121.     IF field = NIL THEN field := obj ELSE last.next := obj END;
  1122.     last := obj
  1123.   END
  1124. END ReadFields;
  1125.  
  1126. PROCEDURE ReadFP(VAR par: Object; VAR nofArgs: LONGINT);
  1127.   VAR obj, last: Object; typ: Struct; n, a0, a1: LONGINT; name: Name;
  1128. BEGIN
  1129.   par := NIL; ReadInt(nofArgs); n := nofArgs;
  1130.   WHILE n > 0 DO
  1131.     ReadName(name); ReadStruct(typ); ReadInt(a0); ReadInt(a1);
  1132.     IF ODD(a1) THEN NewObject(obj, name, VarPar)
  1133.     ELSE NewObject(obj, name, Var)
  1134.     END;
  1135.     obj.typ := typ; obj.a0 := a0; obj.a1 := a1 DIV 2;
  1136.     IF par = NIL THEN par := obj ELSE last.next := obj END;
  1137.     last := obj; DEC(n)
  1138.   END
  1139. END ReadFP;
  1140.  
  1141. PROCEDURE ReadStruct(VAR typ: Struct);
  1142. VAR form: LONGINT; htyp: Struct; name: Name; obj, mod: Object;
  1143. BEGIN
  1144.   ReadInt(form);
  1145.   IF form <= 0 THEN (* struct reference or NIL *) typ := LStruct[-form]
  1146.   ELSE (* first occurence *)
  1147.     NewStruct(htyp, SHORT(form)); ReadName(name);
  1148.     IF name # "" THEN (* named type *)
  1149.       NewObject(obj, name, Type); obj.marked := TRUE; obj.typ := htyp;
  1150.       htyp.obj := obj; ReadMod(mod); InsertImport(obj, mod.link);
  1151.       typ := obj.typ
  1152.     ELSE typ := htyp
  1153.     END;
  1154.     IF nofStructs < MaxNofStructs THEN
  1155.       LStruct[nofStructs] := typ; INC(nofStructs)
  1156.     ELSE err(228) (* to many imported types *)
  1157.     END;
  1158.     ReadStruct(htyp.base);
  1159.     CASE form OF
  1160.     | Proc:
  1161.       OpenScope(htyp.link, 0); ReadFP(htyp.link.next, htyp.len);
  1162.       CloseScope; htyp.size := 1
  1163.     | Array: ReadInt(htyp.len); ReadInt(htyp.size)
  1164.     | DynArr: ReadInt(htyp.size)
  1165.     | Record:
  1166.       OpenScope(htyp.link, 0); ReadFields(htyp.link.next); CloseScope;
  1167.       ReadInt(htyp.size);
  1168.       IF htyp.base # NIL THEN
  1169.         htyp.len := htyp.base.len+1; htyp.link.link := htyp.base.link
  1170.       ELSE htyp.len := 0
  1171.       END
  1172.     | Pointer: typ.size := 1
  1173.     END
  1174.   END
  1175. END ReadStruct;
  1176.  
  1177. PROCEDURE ReadObjects(scope: Object);
  1178.   VAR mode: LONGINT; obj: Object; typ: Struct; name: Name;
  1179. BEGIN
  1180.   LOOP (* read all objects *)
  1181.     ReadInt(mode);
  1182.     IF mode = Undef THEN EXIT
  1183.     ELSIF mode = Type THEN
  1184.       ReadName(name);
  1185.       IF name # "" THEN (* alias type *)
  1186.         NewObject(obj, name, Type); ReadStruct(obj.typ);
  1187.         InsertImport(obj, scope)
  1188.       ELSE (* other types *) ReadStruct(typ)
  1189.       END
  1190.     ELSE
  1191.       ReadName(name); NewObject(obj, name, SHORT(mode));
  1192.       ReadStruct(obj.typ);
  1193.       IF mode = Const THEN
  1194.         IF obj.typ.form = String THEN ReadString(obj.b0, obj.b1)
  1195.         ELSIF obj.typ.form = LReal THEN ReadInt(obj.b0); ReadInt(obj.b1)
  1196.         ELSE ReadInt(obj.b0)
  1197.         END
  1198.       ELSIF obj.mode = Var THEN ReadInt(obj.a0); obj.mode := XVar
  1199.       ELSIF obj.mode = LProc THEN
  1200.         OpenScope(obj.link, 0); ReadFP(obj.link.next, obj.b0); CloseScope;
  1201.         obj.mode := XProc
  1202.       ELSIF obj.mode = IProc THEN
  1203.         OpenScope(obj.link, 0); ReadFP(obj.link.next, obj.b0); CloseScope
  1204.       END;
  1205.       InsertImport(obj, scope)
  1206.     END
  1207.   END
  1208. END ReadObjects;
  1209.  
  1210. PROCEDURE EnterStruct(typ: Struct);
  1211.   (* Enters a predefined type into the LStruct table *)
  1212.  
  1213. BEGIN
  1214. IF impName = "SYSTEM" THEN Insert(mod, impName, Mod); mod.link := system
  1215. ELSE OpenRider(R, impName, res);
  1216. IF res < 0 THEN (*
  1217. no error occured
  1218.  *)
  1219. LStruct[0] := NIL; EnterStruct(stringTyp);
  1220. EnterStruct(undefTyp); EnterStruct(noTyp); EnterStruct(boolTyp); EnterStruct(charTyp);
  1221. EnterStruct(sIntTyp); EnterStruct(intTyp); EnterStruct(lIntTyp); EnterStruct(setTyp);
  1222. EnterStruct(realTyp); EnterStruct(lRealTyp); EnterStruct(cmplxTyp); EnterStruct(lCmplxTyp);
  1223. nofLMods := 0; nofStructs := firstStructRef;
  1224. ReadMod(mod0); ReadObjects(mod0.link);
  1225. Insert(mod, substName, Mod);
  1226. mod.b0 := mod0.b0; mod.mnolev := mod0.mnolev; mod.link := mod0.link
  1227. ELSE err(res)
  1228. END
  1229. END
  1230. END Import;
  1231.  
  1232. (* export *)
  1233.  
  1234. PROCEDURE Export*
  1235.   (mod: Object; VAR buf: ARRAY OF CHAR; VAR len: LONGINT; VAR new: BOOLEAN);
  1236.  
  1237.   VAR pos: LONGINT; nofLMods, nofStructs: INTEGER;
  1238.  
  1239.   PROCEDURE^ WriteStruct(typ: Struct);
  1240.  
  1241.   PROCEDURE Write(ch: CHAR);
  1242.   BEGIN buf[pos] := ch; INC(pos)
  1243.   END Write;
  1244.  
  1245.   PROCEDURE WriteInt(i: LONGINT);
  1246.     (* Writes integers in a compacted form [Te90] *)
  1247.   BEGIN
  1248.     WHILE (i < -64) OR (i > 63) DO
  1249.       Write(CHR(i MOD 128 + 128)); i := i DIV 128
  1250.     END;
  1251.     Write(CHR(i MOD 128))
  1252.   END WriteInt;
  1253.  
  1254.   PROCEDURE WriteName(VAR name: ARRAY OF CHAR);
  1255.   (* Writes a name terminated with 0X *)
  1256.  
  1257.   PROCEDURE WriteString(pos: LONGINT);
  1258.   (* Writes the string terminated with 0X at position pos of the scanner
  1259.      string buffer *)
  1260.  
  1261.   PROCEDURE WriteKey(x: LONGINT);
  1262.     (* Writes an integer in uncompacted form *)
  1263.  
  1264.   PROCEDURE WriteMod(mod: Object);
  1265.   BEGIN
  1266.     IF mod.b1 < 0 THEN (* first occurence *)
  1267.       mod.b1 := nofLMods; INC(nofLMods);
  1268.       WriteInt(Mod); WriteKey(mod.b0); WriteName(mod.name)
  1269.     ELSE WriteInt(-mod.b1)
  1270.     END
  1271.   END WriteMod;
  1272.  
  1273.   PROCEDURE WriteFields(field: Object);
  1274.   BEGIN
  1275.     WHILE field # NIL DO
  1276.       IF field.marked THEN
  1277.         WriteName(field.name); WriteStruct(field.typ); WriteInt(field.a0)
  1278.       END;
  1279.       field := field.next
  1280.     END;
  1281.     Write(0X)
  1282.   END WriteFields;
  1283.  
  1284.   PROCEDURE WriteFP(par: Object; nofArgs: LONGINT);
  1285.   BEGIN
  1286.     WriteInt(nofArgs);
  1287.     WHILE nofArgs > 0 DO
  1288.       WriteName(par.name); WriteStruct(par.typ); WriteInt(par.a0);
  1289.       IF par.mode = VarPar THEN WriteInt(par.a1*2 + 1)
  1290.       ELSE WriteInt(par.a1*2) END;
  1291.       par := par.next; DEC(nofArgs)
  1292.     END
  1293.   END WriteFP;
  1294.  
  1295.   PROCEDURE WriteStruct(typ: Struct);
  1296.     VAR name: Name;
  1297.   BEGIN
  1298.     IF typ = NIL THEN WriteInt(0)
  1299.     ELSIF typ.ref > 0 THEN (* already marked *) WriteInt(-typ.ref)
  1300.     ELSE (* first occurence *)
  1301.       WriteInt(typ.form); typ.ref := nofStructs; INC(nofStructs);
  1302.       IF typ.obj # NIL THEN (* named type *)
  1303.         name := typ.obj.name;
  1304.         IF ~typ.obj.marked THEN (* invisible type *)
  1305.           name[0] := CHR(ORD(name[0]) - ORD("@"))
  1306.         END;
  1307.         WriteName(name); WriteMod(GMod[-typ.obj.mnolev])
  1308.       ELSE Write(0X)
  1309.       END;
  1310.       WriteStruct(typ.base);
  1311.       CASE typ.form OF
  1312.       | Proc: WriteFP(typ.link.next, typ.len)
  1313.       | Array: WriteInt(typ.len); WriteInt(typ.size)
  1314.       | DynArr: WriteInt(typ.size)
  1315.       | Record: WriteFields(typ.link.next); WriteInt(typ.size)
  1316.       | Pointer:
  1317.       END
  1318.     END
  1319.   END WriteStruct;
  1320.  
  1321.   PROCEDURE WriteObjects(obj: Object);
  1322.   BEGIN
  1323.     WHILE obj # NIL DO
  1324.       IF obj.marked THEN
  1325.         WriteInt(obj.mode);
  1326.         IF (obj.mode # Type) OR (obj.typ.obj # obj) THEN
  1327.           (* no-type or alias type *) WriteName(obj.name)
  1328.         ELSE (* other type *) Write(0X)
  1329.         END;
  1330.         WriteStruct(obj.typ);
  1331.         IF obj.mode = Const THEN
  1332.           IF obj.typ.form = String THEN WriteString(obj.b0)
  1333.           ELSIF obj.typ.form = LReal THEN WriteInt(obj.b0); WriteInt(obj.b1)
  1334.           ELSE WriteInt(obj.b0)
  1335.           END
  1336.         ELSIF obj.mode = Var THEN WriteInt(obj.a0)
  1337.         ELSIF obj.mode IN {LProc, IProc} THEN WriteFP(obj.link.next, obj.b0)
  1338.         END
  1339.       END;
  1340.       obj := obj.next
  1341.     END;
  1342.     WriteInt(Undef) (* termination tag *)
  1343.   END WriteObjects;
  1344.  
  1345.   PROCEDURE Compare(VAR buf: ARRAY OF CHAR; len: LONGINT; VAR new: BOOLEAN);
  1346.     VAR res: INTEGER; i: LONGINT; R: Files.Rider; ch: CHAR;
  1347.         prefix: ARRAY 5 OF CHAR;
  1348.   BEGIN
  1349.     OpenRider(R, mod.name, res); new := TRUE;
  1350.     IF res < 0 THEN
  1351.       Files.ReadBytes(R, prefix, LEN(prefix)); Files.Read(R, ch);
  1352.       i := LEN(prefix);
  1353.       WHILE (i < len) & (buf[i] = ch) DO Files.Read(R, ch); INC(i) END;
  1354.       IF i = len THEN (* same symbol table => use old key *)
  1355.         i := 0; WHILE i < LEN(prefix) DO buf[i] := prefix[i]; INC(i) END;
  1356.         new := FALSE
  1357.       END
  1358.     END
  1359.   END Compare;
  1360.  
  1361. BEGIN
  1362.   pos := 0; nofLMods := 0; nofStructs := firstStructRef;
  1363.   WriteMod(mod); WriteObjects(mod.link.next);
  1364.   Compare(buf, pos, new)
  1365. END Export;
  1366.  
  1367.